Manage domain properties
!! Manage domain properties !|author: <a href="mailto:giovanni.ravazzani@polimi.it">Giovanni Ravazzani</a> ! license: <a href="http://www.gnu.org/licenses/">GPL</a> ! !### History ! ! current version 1.1 - 11th November 2024 ! ! | version | date | comment | ! |----------|-------------|----------| ! | 1.0 | 27/May/2021 | Original code | ! | 1.1 | 11/Nov/2024 | soil texture map reading added | ! !### License ! license: GNU GPL <http://www.gnu.org/licenses/> ! !### Module Description ! Module to manage domain properties: ! ! * Simulation extent and spatial reference system ! [[DomainProperties(module):mask(variable)]] ! ! * Ground albedo ! [[DomainProperties(module):albedoGround(variable)]] ! ! * Land cover ! [[DomainProperties(module):landcover(variable)]] ! ! * Soil texture ! [[DomainProperties(module):soilTexture(variable)]] ! ! list of soil texture classes and corresponding id: ! ! | id | Soil texture class | ! |---------|--------------------| ! | 0 | texture unknown | ! | 1 | clay | ! | 2 | silty clay | ! | 3 | sandy clay | ! | 4 | clay loam | ! | 5 | silty clay loam | ! | 6 | sandy clay loam | ! | 7 | loam | ! | 8 | silty loam | ! | 9 | sandy loam | ! | 10 | silt | ! | 11 | loamy sand | ! | 12 | sand | ! ! MODULE DomainProperties ! Modules used: USE DataTypeSizes, ONLY: & !Imported type definitions: short, long, float USE LogLib, ONLY: & ! Imported routines: Catch USE IniLib, ONLY : & !Imported types: IniList, & !Imported routines: IniOpen, SectionIsPresent, & IniClose USE GridLib, ONLY: & !Imported type definitions: grid_integer, grid_real, & !Imported routines: NewGrid USE GridOperations, ONLY: & !Imported routines GridByIni, CRSisEqual USE Morphology, ONLY: & !imported routines: Centroid USE GeoLib, ONLY: & !Imported variables: point1, point2, & !Imported routines: DecodeEPSG, Convert USE Units, ONLY : & !imported parameters: degToRad IMPLICIT NONE !Global declarations: TYPE (grid_integer) :: mask !! define domain analysis and spatial reference system TYPE (grid_real) :: albedoGround !!ground albedo TYPE (grid_real) :: albedo !! albedo (state variable) TYPE (grid_integer) :: landcover !!landcover, assume Corine Land Cover convention codes. TYPE (grid_integer) :: soilTexture !!soil texture according to USDA classification system REAL (KIND = float) :: latCentroid !!latitude of centroid of domain analysis LOGICAL :: mask_loaded = .FALSE. LOGICAL :: albedo_loaded = .FALSE. LOGICAL :: landcover_loaded = .FALSE. LOGICAL :: soil_texture_loaded = .FALSE. !Public routines PUBLIC :: DomainInit !Local (i.e. private) declarations TYPE (IniList), PRIVATE :: domainini !Local routines !======= CONTAINS !======= ! Define procedures contained in this module. !============================================================================== !| Description: ! Load domain properties SUBROUTINE DomainInit & ! ( inifile ) IMPLICIT NONE ! arguments with intent (in) CHARACTER (LEN = *), INTENT(IN) :: inifile !!name of configuration file ! local declarations INTEGER (KIND = short) :: option !-------------------------end of declarations---------------------------------- !open and load configuration file CALL IniOpen (inifile, domainini) !read domain mask IF (SectionIsPresent('mask', domainini)) THEN CALL GridByIni (domainini, mask, section = 'mask') mask_loaded = .TRUE. ELSE !basin is mandatory: stop the program CALL Catch ('error', 'DomainProperties', & 'error in loading mask: ' , & argument = 'section not defined in ini file' ) END IF !read albedo IF (SectionIsPresent('albedo', domainini)) THEN CALL GridByIni (domainini, albedoGround, section = 'albedo') IF ( .NOT. CRSisEqual (mask = mask, grid = albedoGround, & checkCells = .TRUE.) ) THEN CALL Catch ('error', 'DomainProperties', & 'wrong spatial reference in albedo' ) END IF !initialise albedo state variable as albedoGround CALL NewGrid (albedo, albedoGround) albedo_loaded = .TRUE. END IF !read land cover IF (SectionIsPresent('land-cover', domainini)) THEN CALL GridByIni (domainini, landcover, section = 'land-cover') IF ( .NOT. CRSisEqual (mask = mask, grid = landcover, & checkCells = .TRUE.) ) THEN CALL Catch ('error', 'DomainProperties', & 'wrong spatial reference in land cover' ) END IF landcover_loaded = .TRUE. END IF !read soil texture IF (SectionIsPresent('soil-texture', domainini)) THEN CALL GridByIni (domainini, soilTexture, section = 'soil-texture') IF ( .NOT. CRSisEqual (mask = mask, grid = soilTexture, & checkCells = .TRUE.) ) THEN CALL Catch ('error', 'DomainProperties', & 'wrong spatial reference in soil texture' ) END IF soil_texture_loaded = .TRUE. END IF !compute centroid of mask CALL Centroid (mask, point1) point2 % system = DecodeEPSG (4326) CALL Convert (point1, point2) latCentroid = point2 % northing latCentroid = latCentroid * degToRad !close ini CALL IniClose (domainini) RETURN END SUBROUTINE DomainInit END MODULE DomainProperties